home *** CD-ROM | disk | FTP | other *** search
- NAME ccsker
- ; File CCSKER.ASM
-
- ;CHINESE
- ifdef MSDOS
- include mssker.dat
- else
- include ccsker.dat
- endif
-
- code segment public 'code'
- extrn cmblnk:near, locate:near, logout:near, mail:near
- extrn bye:near, telnet:near, finish:near, comnd:near, prompt:near
- extrn read:near, remote:near, send:near, status:near, get:near
- extrn dodisk:near, serrst:near, setcom:near, dtrlow:near
- extrn clscpi:near, clscpt:near, getbaud:near
- extrn dodef:near, setcpt:near, docom:near, shomodem:near
- extrn server:near, lclini:near, shokey:near, shomac:near, shosta:near
- extrn packlen:near, strlen:near, strcpy:near, shserv:near
- extrn strcat:near, prtasz:near, shorx:near, lnout:near
- extrn scout:near,scinp:near,scpau:near,scecho:near,scclr:near
- extrn scxmit:near, scwait:near, srvdsa:near, srvena:near
- extrn shcom:near, shlog:near, shpro:near, shterm:near, shscpt:near
- extrn shfile:near, takopen:near, takclos:near, ask:near, assign:near
- extrn goto:near, screinp:near, ifcmd:near, isdev:near
- extrn chkos:near ; Jun. 1990
- assume cs:code, ds:datas, ss:cstack, es:nothing
-
- START PROC FAR
- mov ax,datas ; Initialize DS
- mov ds,ax
- mov psp,es ; remember psp address
-
- mov ah,dosver
- int dos
- mov dosnum,al ; remember dos version
- cmp dosnum,2 ; earlier than DOS 2.0?
- jge start1 ; ge = no
- mov ah,prstr
- ; mov dx,offset erms34 ; Complain
- mcmsg erms34, cerms34
- int dos
- mov ax,psp ; set up exit for DOS 1
- push ax ; push the segment
- mov ax,0 ; and the IP
- push ax ; make return addr of psp:0 for DOS 1
- ret ; and return far to exit now
- start1:
- call chkos ; check if MS-DOS or CC-DOS ? Jun.1990
- mov ah,prstr
- mov dx,offset machnam ; print machine name
- int dos
- mov ah,prstr ; Print the version header
- ; mov dx,offset versio
- mcmsg versio, cversio
- int dos
- mov ah,setdma ; Set disk transfer address
- mov dx,offset buff
- int dos
-
- call setint
- mov ah,gcurdsk ; Get current disk
- int dos
- inc al ; We want 1 == A (not zero)
- mov curdsk,al
- mov origd,al ; Remember original disk we started on
- mov si,offset orgdir ; place for directory path w/o drive code
- add al,'A'-1 ; make al alphabetic disk drive again
- mov [si],al ; put it into original path descriptor
- inc si
- mov byte ptr [si],':' ; add drive specifier too
- inc si
- mov byte ptr [si],'\' ; add root indicator as well
- inc si
- mov ah,gcd ; get current directory (path really)
- xor dl,dl ; use current drive
- int dos
- call getpath ; get the path from the environment
- call getcsp ; get comspec from environment
- call memini ; init our memory usage
- call lclini ; do local initialization
- call packlen ; Packet length in case do server comand
- mov ah,gswitch
- mov al,0 ; pick up switch character
- int dos
- mov slashc+1,dl
- mov al,maxtry ; limit # packet retries
- and al,3fh ; 63 max
- mov maxtry,al
- shl al,1 ; times two. I packets get more tries
- mov imxtry,al ; keep that much
- add al,maxtry ; try three times
- js start2 ; s = sign bit set, too large
- mov imxtry,al ; imxtry = 3 * maxtry
- start2: mov comand.cmrprs,offset krmend ; address to go to on reparse
- mov comand.cmostp,sp ; Save for reparse too
- call gcmdlin ; read command line
- cmp taklev,0 ; in a Take file?
- jne start3 ; ne = yes, skip help msg
- mov ah,prstr
- ; mov dx,offset hlpmsg
- mcmsg hlpmsg,chlpmsg
- int dos
- start3: call serrst ; reset serial port (if active)
- call rdinit ; read kermit init file
-
- ; This is the main KERMIT loop. It prompts for and gets the users commands
-
- kermit: mov ax,ds
- mov es,ax ; make sure this addresses data segment
- cmp taklev,0 ; keep port open between script cmds
- jne kermt1 ; ne = in Take or Macro
- call serrst ; reset serial port for CTTY DOS use
- kermt1: mov dx,prmptr ; get prompt
- call chkos ; check if MS-DOS or CC-DOS ? Jun.1990
- call prompt ; Prompt the user, set reparse address
- mov pack.state,0 ; Clear the state
- mov flags.cxzflg,0 ; Reset each time
- and flags.remflg,not dserver ; turn off server mode bit
- mov ah,inichk ; Original or set checksum length
- mov trans.chklen,ah ; Reset just in case
- mov dx,offset comtab
- ; mov bx,offset tophlp
- mcmsgb tophlp,ctophlp
- cmp flags.extflg,0 ; Check if the exit flag is set
- jne krmend ; If so jump to KRMEND
- mov comand.cmcr,1 ; Allow bare CR's
- mov ah,cmkey
- mov comand.impdo,1 ; allow implied "DO macro"
- call comnd
- jmp kermt3
- nop
- mov comand.impdo,0 ; only on initial keyword, not here
- mov comand.cmcr,0 ; no more bare CR's
- call bx ; Call the routine returned
- jmp kermt3
- nop
- cmp flags.extflg,0 ; Check if the exit flag is set
- jne krmend ; If so jump to KRMEND
- jmp short kermt5 ; Do it again
-
- kermt3: mov kstatus,8 ; global status
- cmp flags.cxzflg,'C' ; got here via Control-C?
- jne kermt7 ; ne = no
- kermt4: cmp flags.extflg,0 ; Check if the exit flag is set
- jne kermt5 ; ne = yes, skip msg, do cleanup
- ; mov dx,offset ermes3 ; Say command not executed
- mcmsg ermes3,cermes3
- mov ah,prstr ; print the error message in dx
- int dos
- kermt5: cmp flags.cxzflg,'C' ; user Control-C abort?
- jne kermt7 ; ne = no, do normal operations
- cmp taklev,0 ; in a Take file?
- je kermt7 ; e = no
- call takclos ; close take file, release buffer
- jmp kermt5 ; close any other take files
- kermt7: mov flags.nmoflg,0 ; Reset filename override flag
- mov flags.getflg,0 ; May as well do this one
- cmp flags.extflg,0 ; Check if the exit flag is set
- jne krmend ; ne = yes, Exit now
- jmp kermit ; get next command
-
- krmend: call serrst ; Just in case the port wasn't reset
- test flags.capflg,0FFH ; Logging active?
- jz krmend2 ; z = no
- call clscpi ; close log files
- nop ; this skip returns..
- nop
- nop
- krmend2:cmp lclexit,0 ; sys dependent routines want service?
- je krmend3 ; e = no
- mov bx,lclexit ; addr of sys dependent exit routine
- call bx ; call it
- krmend3:mov dl,origd ; Original disk drive
- dec dl ; Want A == 0
- mov ah,seldsk ; Reset original disk just in case
- int dos
- mov dx,offset orgdir ; restore original directory
- mov ah,chdir
- int dos
- mov dx,offset in3ad ; restore Control-C interrupt vector
- mov al,23H ; interrupt 23H
- mov ah,25H ; set interrupt vector
- int dos ; ah, that's better
- mov dx,offset ceadr ; DOS's Critical Error handler
- mov al,24h ; interrupt 24h
- mov ah,25h ; do replacement (put it back)
- int dos
- mov ah,4cH ; terminate process
- mov al,errlev ; return error level
- int dos
- ret
- START ENDP
-
- ; This is the 'EXIT' command. It leaves KERMIT and returns to DOS
-
- EXIT PROC NEAR
- mov ah,cmcfm
- call comnd ; Get a confirm
- jmp r
- nop
- mov flags.extflg,1 ; Set the exit flag
- jmp rskp ; Then return to system
- EXIT ENDP
-
- ; TAKE commands from a file, and allow a path name
- TAKE PROC NEAR
- mov kstatus,0 ; global status, success
- cmp taklev,maxtak ; Hit our limit?
- jl take1 ; Continue if still OK
- mov ah,prstr
- ;mov dx,offset erms30 ; Complain
- mcmsg erms30, cerms30
- int dos
- ret
- take1: mov dx,offset tmpbuf ; work buffer
- mov tmpbuf,0
- ; mov bx,offset filmsg ; Help in case user types "?"
- mcmsgb filmsg,cfilmsg
- mov ah,cmfile ; get file name
- call comnd
- jmp r
- nop
- mov ah,cmcfm
- call comnd
- jmp r
- nop
- mov ax,offset tmpbuf ; point to name again
- cmp tmpbuf,0 ; empty filespec?
- jne take2 ; ne = no
- mov ah,prstr
- ; mov dx,offset ermes1 ; say more parameters needed
- mcmsg ermes1,cermes1
- int dos
- jmp rskp
- ; TAKE2: enter with ax=filename ptr
- TAKE2: call spath ; is it around?
- jc take3 ; no, go complain
- mov dx,ax ; point to name from spath
- mov ah,open2 ; 2.0 open call
- cmp dosnum,2 ; above DOS 2?
- mov al,0 ; open for reading
- jna take2a ; na = no, so no shared access
- mov al,0+40h ; open for reading, deny none
- take2a: int dos
- jnc take4 ; nc = opened ok, keep going
- mov ax,dx ; recover filename pointer
- take3: push ax
- mov ah,prstr
- ; mov dx,offset erms31
- mcmsg erms31, cerms31
- int dos
- pop ax
- mov dx,ax ; asciiz file name
- call prtasz ; display it
- mov kstatus,8 ; global status
- jmp rskp ; we've done all error displays
- ; TAKE4: enter with ax=filename ptr
- TAKE4: call takopen ; open take buffer in macro space
- jc take6 ; c = failure
- push bx
- mov bx,takadr ; get current frame ptr
- mov [bx].takhnd,ax ; save file handle
- mov [bx].taktyp,0feh ; mark as 2.0 file handle
- pop bx
- cmp flags.takflg,0 ; echoing Take files?
- je take5 ; e = no
- mov ah,prstr
- mov dx,offset crlf
- int dos
- take5: call takrd ; Get a buffer full of data
- take6: jmp rskp
- TAKE ENDP
-
- TAKRD PROC NEAR
- push ax
- push bx
- push cx
- push dx
- mov bx,takadr
- cmp [bx].taktyp,0feh ; get type of take (file?)
- jne takrd1 ; ne = no, do not read from disk
- mov dx,[bx].takbuf ; address of buffer to read into
- inc dx ; skip count byte in takbuf
- mov cx,dmasiz ; # of bytes to read
- push si
- mov si,dx ; fill buffer with spaces for
- takrd0: mov byte ptr [si],' ' ; Show Macro
- inc si
- loop takrd0
- pop si
- mov cx,dmasiz
- push bx ; save frame address
- mov bx,[bx].takhnd ; file handle is stored here
- mov ah,readf2 ; 2.0 read call
- int dos
- pop bx ; restore frame address
- jnc takrd2 ; nc = successful read
- takrd1: mov ax,0 ; error, say zero bytes read
- takrd2: mov [bx].takcnt,ax ; number of bytes read
- mov ax,[bx].takbuf
- inc ax ; skip count byte in takbuf
- mov [bx].takptr,ax ; first new character
- pop dx
- pop cx
- pop bx
- pop ax
- ret
- TAKRD ENDP
-
- ; TAKE-QUIT Exit all Take files immediately but gracefully
-
- TAKEQIT PROC NEAR
- mov ah,cmcfm
- call comnd
- jmp r
- nop
- takqit1:mov ch,0
- mov cl,taklev ; number of Take levels active
- jcxz takqit2 ; z = none
- call takclos ; close current Take file
- jmp short takqit1 ; repeat until all are closed
- takqit2:jmp rskp
- TAKEQIT ENDP
-
- ; put mskermit.ini onto take stack if it exists. Just like
- ; the take command, except it doesn't read a filename
-
- rdinit proc near ; read kermit init file..
- mov ax,offset ininm2 ; default name to try
- cmp decbuf,0 ; alternate init file given?
- je rdini1 ; ne = no
- mov ax,offset decbuf ; yes, use it
- call take2 ; Let Take do error msgs
- nop
- nop
- nop
- ret
- rdini1: call spath ; is it around?
- jc rdini2 ; no, ignore file
- mov dx,ax ; point to name from spath
- mov ah,open2 ; 2.0 open call
- mov al,0 ; open for reading
- cmp dosnum,2 ; above DOS 2?
- jna rdini1a ; na = no, so no shared access
- mov al,0+40h ; open for reading, deny none
- rdini1a:int dos
- jc rdini2 ; c = no ini file found, ignore
- call take4 ; use TAKE command to complete work
- nop ; ignore errors
- nop
- nop
- rdini2: ret
- rdinit endp
-
- ; Get command line into a Take macro buffer. Allow "-f filspec" to override
- ; normal mskermit.ini initialization filespec, allow command "stay" to
- ; suppress automatic exit to DOS at end of command line execution. [jrd]
-
- gcmdlin proc near
- mov word ptr decbuf,0 ; storage for new init filename
- push es
- cld
- mov es,psp ; address psp
- mov ch,0
- mov cl,es:byte ptr[cline] ; length of cmd line from DOS
- jcxz gcmdl1 ; z = empty line
- mov si,cline+1 ; point to actual line
- gcmdl0: cmp byte ptr es:[si],' ' ; skip over leading whitespace
- ja gcmdl2 ; a = non-whitespace
- inc si
- loop gcmdl0 ; fall through on all whitespace
- gcmdl1: jmp gcmdl14 ; common exit jump point
- gcmdl2: inc cx ; include DOS's c/r
- call takopen ; open take buffer in macro space
- mov bx,takadr
- mov byte ptr [bx].taktyp,0ffh ; mark as a macro
- mov [bx].takcnt,0 ; length of text
- mov di,[bx].takbuf ; offset of buffer, from takopen
- inc di ; skip count byte
- mov ax,ds
- mov dx,es ; swap ds and es
- mov es,ax
- mov ds,dx ; ds = PSP, es = datas
- gcmdl3: cmp cx,0 ; anything left?
- jbe gcmdl10 ; be = no
- lodsb ; get a byte
- dec cx ; one less char in input string
- cmp al,',' ; comma?
- jne gcmdl4 ; no, keep going
- mov al,cr ; convert to cr
- jmp gcmdl9 ; store it
- gcmdl4: cmp al,'-' ; starting a flag?
- jne gcmdl9 ; ne = no
- mov ah,byte ptr[si] ; get flag letter
- or ah,20h ; convert to lower case
- cmp ah,'f' ; 'f' for init file replacement?
- jne gcmdl9 ; ne = no
- mov ah,byte ptr[si+1] ; need space or tab separator
- cmp ah,' ' ; separator?
- ja gcmdl9 ; a = no, not a flag
- ; strip out and analyze flag info
- inc si ; point at separator
- dec cx
- gcmdl5: cmp cx,0 ; anything to read?
- jle gcmdl10 ; le = exhausted supply
- lodsb ; get filespec char from psp
- dec cx ; one less char in source buffer
- cmp al,' ' ; in whitespace?
- jbe gcmdl5 ; be = yes, scan it off
- dec si ; backup to real text
- inc cx
- ; copy filspec to buffer decbuf
- push di ; save current destination pointer
- lea di,decbuf ; where filespec part goes
- mov word ptr es:[di],0 ; plant safety terminator
- gcmdl6: lodsb ; get filespec char
- dec cx ; one less available
- cmp cx,0 ; any chars left?
- jle gcmdl7 ; le = no
- cmp al,' ' ; in printables?
- jbe gcmdl7 ; be = no, all done
- cmp al,',' ; comma command separator?
- je gcmdl7 ; e = yes, all done
- stosb ; store filespec char
- mov byte ptr es:[di],0 ; end filespec on a null
- jmp short gcmdl6
- gcmdl7: pop di ; recover macro register
- dec si ; compensate for last read above
- inc cx
- gcmdl8: cmp cx,0 ; strip trailing whitespace
- jbe gcmdl10 ; be = nothing left
- lodsb
- dec cx
- cmp al,' ' ; white space?
- jbe gcmdl8 ; be = yes, strip it
- cmp al,',' ; at next command?
- je gcmdl10 ; e = yes, skip our own comma
- dec si ; back up to reread the char
- inc cx
- jmp gcmdl3 ; read more command text
- ; end of flag analysis
- gcmdl9: stosb ; deposit most recent char
- gcmdl10:cmp cx,0 ; anything left to read?
- jg gcmdl3 ; g = yes, loop
- ;
- mov ax,datas ; restore segment registers
- mov ds,ax
- mov es,ax ; return to ds=datas, es=datas
- mov si,[bx].takbuf ; get address of text field
- inc si ; skip count byte
- mov cx,di ; current end pointer, (save di)
- sub cx,si ; current ptr minus start offset
- mov [bx].takcnt,cx
- cmp cx,0
- jg gcmdl11 ; material at hand
- call takclos ; empty take file
- jmp gcmdl14 ; finish up
- ; scan for command "stay"
- gcmdl11:lodsb ; get a byte, cx and si are set above
- dec cx
- cmp al,' ' ; separator?
- jbe gcmdl12 ; be = yes, keep looking
- cmp al,',' ; comma separator?
- je gcmdl12 ; e = yes
- mov ah,al ; get first byte
- lodsb ; second byte after separator
- dec cx
- or ax,2020h ; convert to lower case
- cmp ax,'st' ; first two letters of stay
- jne gcmdl12 ; ne = no match
- lodsw ; next two letters (stay vs status)
- sub cx,2
- or ax,2020h ; convert to lower case
- cmp ax,'ya' ; same as our pattern?
- jne gcmdl12 ; ne = no match
- ; check for separator or end of macro
- cmp cx,0 ; at end of macro?
- jle gcmdl13 ; yes, consider current match correct
- cmp byte ptr[si],' ' ; next char is a separator?
- jbe gcmdl13 ; be = yes, found correct match
- cmp byte ptr[si],',' ; or comma separator?
- je gcmdl13 ; e = yes
- gcmdl12:cmp cx,0 ; done yet? ("stay" not found)
- jg gcmdl11 ; g = not yet, look some more
- mov si,offset eexit ; append command "exit"
- mov cx,leexit ; length of string "exit"
- add [bx].takcnt,cx
- rep movsb ; copy it into the macro
- gcmdl13:mov ax,[bx].takbuf
- inc ax ; skip count byte
- mov [bx].takptr,ax ; init buffer ptr
- gcmdl14:pop es
- ret
- gcmdlin endp
-
- ; Enter with ax pointing to file name. Searches path for given file,
- ; returns with ax pointing to whole name, or carry set if file can't be found.
- SPATH proc near
- call isfile ; does it exist as it is?
- jc spath0 ; c = no, prepend path elements
- test byte ptr filtst.dta+21,10H ; subdirectory name?
- jnz spath0 ; nz = yes, not desired file
- clc
- ret
- spath0: push es ; save es around work
- push bx
- push si
- push di
- mov bx,ax ; save filename pointer in bx
- mov si,ax
- mov dl,0 ; no '\' seen yet
- cld
- spath1: lodsb
- cmp al,2fh ; contains fwd slash path characters?
- je spath1a
- cmp al,5ch ; or backslash?
- jne spath2 ; no, keep going
- spath1a:mov dl,1 ; remember we've seen them
- spath2: or al,al
- jnz spath1 ; copy name in
- or dl,dl ; look at flag
- jz spath3 ; no path, keep looking
- jmp spath9 ; embedded path, fail
-
- spath3: mov si,pthadr ; offset of PATH= string in environment
- mov es,psp
- mov di,es:word ptr[env] ; pick up environment segment
- mov es,di
- spath4: cmp byte ptr es:[si],0 ; end of PATH= string?
- je spath9 ; e = yes, exit loop
- mov di,offset decbuf+64 ; place to put name
- spath5: mov al,byte ptr es:[si] ; get a byte from environment string
- inc si
- cmp al,';' ; end of this part?
- je spath7 ; yes, break loop
- cmp al,0 ; maybe end of string?
- jne spath6 ; no, keep going
- dec si ; back up to null for later rereading
- jmp short spath7 ; and break loop
- spath6: mov byte ptr [di],al ; else stick in dest string
- inc di
- jmp spath5 ; and continue
- spath7: push si ; save this ptr
- mov si,bx ; this is user's file name
- cmp byte ptr [di-1],2fh ; does path end with switch char?
- je spath8 ; yes, don't put one in
- cmp byte ptr [di-1],5ch ; how about this one?
- je spath8 ; yes, don't put it in
- mov byte ptr [di],5ch ; else add one
- inc di
- spath8: lodsb ; get filename character
- mov byte ptr [di],al ; copy filename char to output buffer
- inc di
- or al,al ; end of string?
- jnz spath8 ; nz = no, copy rest of name
- pop si ; restore postion in path string
- mov ax,offset decbuf+64
- call isfile ; is it a file?
- jc spath4 ; c = no, keep looking
- test byte ptr filtst.dta+21,10H ; subdirectory name?
- jnz spath4 ; nz = yes
- pop di
- pop si
- pop bx
- pop es
- clc
- ret ; return success (carry clear)
- spath9: mov ax,bx ; restore original filename pointer
- pop di ; restore regs
- pop si
- pop bx
- pop es
- stc ; no file found
- ret
- spath endp
-
- ; Put offset of PATH= string in pthadr
- getpath proc near
- push bx
- push cx
- push dx
- mov bx,offset pthnam ; thing to find
- mov cx,pthlen ; length of it
- mov pthadr,0 ; init offset to zero
- call getenv ; get environment value
- mov pthadr,dx
- pop dx
- pop cx
- pop bx
- ret ; and return
- getpath endp
-
- ; copy COMSPEC= environment string into cmspbuf
- getcsp proc near
- push bx
- push cx
- push dx
- push es
- mov bx,offset cmspnam ; find COMSPEC=
- mov cx,cmsplen ; it's length
- call getenv ; get environment offset in dx
- mov di,offset cmspbuf ; where to store string
- mov si,dx ; address of COMSPEC= string
- mov es,psp
- mov bx,es:word ptr[env] ; pick up environment address
- mov es,bx
- push ds ; save ds
- push ds ; make ds point to environment seg
- push es ; make es point to datas segment
- pop ds
- pop es
- cld
- getcs1: lodsb ; get a byte from environment
- cmp al,' ' ; space or less?
- jg getcs2 ; g = no, keep copying
- mov al,0 ; terminate string on spaces etc
- getcs2: stosb ; store it in cmspbuf
- or al,al ; at end of string yet?
- jne getcs1 ; ne = no, keep copying
- pop ds ; recover ds
- pop es
- pop dx
- pop cx
- pop bx
- ret ; and return
- getcsp endp
-
- ; Locate string variable in Environment
- ; bx/ variable to find (incl =), cx/ length of variable name,
- ; dx/ address to store value at
- getenv proc near
- push ax
- push cx
- push si
- push di
- push es
- mov es,psp
- mov ax,es:word ptr[env] ; pick up environment address
- mov es,ax
- mov di,0 ; start at this offset in segment
- geten1: cmp es:byte ptr [di],0 ; end of environment?
- je geten4 ; yes, forget it
- push cx ; save counter
- push di ; and offset
- mov si,bx
- cld
- repe cmpsb ; search for name
- pop di
- pop cx ; restore these
- je geten2 ; found it, break loop
- push cx ; preserve again
- mov cx,0ffffh ; bogus length
- mov al,0 ; marker to look for
- repne scasb ; search for it
- pop cx ; restore length
- jmp geten1 ; loop thru rest of environment
- geten2: add di,cx ; skip to definition
- geten4: mov dx,di ; store offset of string
- pop es
- pop di
- pop si
- pop cx
- pop ax
- ret ; and return
- getenv endp
-
- COMNT PROC NEAR ; COMMENT command
- mov ah,cmtxt
- mov bx,offset tmpbuf
- mov dx,0
- call comnd
- jmp r
- nop
- jmp rskp
- COMNT ENDP
-
- ; change working directory
- cwdir proc near
- mov kstatus,0 ; global status
- mov ah,cmfile
- mov dx,offset tmpbuf
- ; mov bx,offset pthmsg
- mcmsgb pthmsg, cpthmsg
-
- call comnd
- jmp r
- mov ah,cmcfm
- call comnd
- jmp r
- cmp tmpbuf,0 ; anything given?
- jne cwd1 ; ne = yes
- mov ah,prstr
- ; mov dx,offset ermes1 ; say need more
- mcmsg ermes1,cermes1
- int dos
- jmp rskp
- cwd1: mov dl,curdsk ; remember present disk
- mov byte ptr temp,dl
- mov bx,offset tmpbuf ; change of drives, if req'd
- cmp byte ptr [bx+1],':' ; was a drive specified?
- jne cwd2 ; ne = no
- mov dl,[bx] ; get the drive letter
- add bx,2 ; skip drive colon
- and dl,5FH ; make upper case
- sub dl,'A' ; convert to A = 0, etc
- mov ah,seldsk
- int dos ; change disks
- jc cwd3 ; c = failure
- inc dl ; count A = 1 internally
- mov curdsk,dl ; and store it
- cwd2: cmp byte ptr [bx],0 ; anything left?
- je cwd4 ; e = no
- mov dx,bx ; get path string
- mov ah,chdir ; DOS change directory
- int dos
- jnc cwd4 ; nc = success
- ;cwd3: mov dx,offset ermes4 ; failure
- cwd3: mcmsg ermes4,cermes4
- mov ah,prstr
- int dos
- mov dl,byte ptr temp ; get current disk
- dec dl ; A = 0 for DOS
- mov ah,seldsk ; restore it
- int dos
- mov kstatus,8 ; global status
- cwd4: jmp rskp
- cwdir endp
-
-
- ; Erase specified file(s). Add protection of ignore hidden, subdir, volume
- ; label and system files. 9 Jan 86 [jrd]
- DELETE PROC NEAR ; revised for DOS 2.0, incl paths & ?* [jrd]
- mov kstatus,0 ; global status
- mov si,offset delcmd ; del command
- mov di,offset tmpbuf
- call strcpy
- mov dx,offset tmpbuf
- call strlen ; get its length
- add di,cx ; point at terminator
- mov ah,cmfile ; filespec
- mov dx,di ; where to place the file specs
- ; mov bx,offset filmsg ; In case user wants help.
- mcmsgb filmsg,cfilmsg
- call comnd
- jmp r
- nop
- mov temp,ax ; save byte count
- mov ah,cmcfm
- call comnd
- jmp r
- nop
- cmp byte ptr temp+1,0 ; anything given?
- jne delet1 ; ne = yes
- mov ah,prstr
- ; mov dx,offset ermes1 ; say need something
- mcmsg ermes1,cermes1
- int dos
- jmp rskp
-
- delet1: mov dx,offset delcmd ; get length of prefix (del )
- call strlen
- mov ax,offset tmpbuf ; command line so far
- add ax,cx ; bump address to filename field
- call isfile ; and ask if file exists & what kind it is
- jc delet2 ; c = no such file, complain
- test byte ptr filtst.dta+21,1EH; attribute bits: is file protected?
- jz delet3 ; z = no, go ahead
- delet2: mov ah,prstr
- ; mov dx,offset badnam ; give error message
- mcmsg badnam, cbadnam
- int dos
- mov kstatus,8 ; global status
- jmp rskp ; and ignore this command
- delet3: mov si,offset tmpbuf ; del cmd
- jmp crun ; join run cmd from there
- DELETE ENDP
-
- CHKDSK PROC NEAR ; Space command
- mov kstatus,0 ; global status
- mov ah,cmcfm
- call comnd
- jmp r
- mov ah,prstr
- mov dx,offset crlf ; start of message
- int dos
- mov dl,0 ; use current drive
- mov ah,36h ; get disk free space
- int dos
- cmp ax,0ffffh ; error response?
- je chkdsk1 ; e = yes
- mul bx ; sectors/cluster * clusters = sectors
- mov bx,dx ; save high word of sectors (> 64K)
- mul cx ; bytes = sectors * bytes/sector
- push ax ; save low word of bytes
- mov ax,bx ; recall sectors high word
- mov bx,dx ; save current bytes high word
- mul cx ; high word sectors * bytes/sector
- add ax,bx ; new high bytes + old high bytes
- mov dx,ax
- pop ax
- mov di,offset tmpbuf ; work space for lnout
- mov word ptr[di],' ' ; start with two spaces
- add di,2
- call lnout
-
- mov si,offset spcmsg
- cmp isccdos,0 ; if in CCDOS ?
- jz chkdsk0 ; z = No
- mov si,offset cspcmsg
-
- chkdsk0:call strcat ; add text to end of message
- mov dx,offset tmpbuf
- call prtasz ; print asciiz string
- jmp rskp
- chkdsk1:mov ah,prstr
- ; mov dx,offset spcmsg2 ; say drive not ready
- mcmsg spcmsg2, cspcmsg2
- int dos
- mov kstatus,8 ; global status
- jmp rskp
- CHKDSK ENDP
-
- ; Get directory listing
- DIRECT PROC NEAR
- mov kstatus,0 ; global status
- mov si,offset dircmd ; dir command
- mov di,offset tmpbuf
- call strcpy
- mov dx,offset tmpbuf
- call strlen ; get its length
- add di,cx ; point at terminator
- mov ah,cmtxt ; parse with cmtxt so we can have paths
- mov bx,di ; next available byte
- ; mov dx,offset filmsg ; In case user wants help.
- mcmsg filmsg, cfilmsg
- call comnd
- jmp r
- mov byte ptr [bx],0 ; plant terminator
- mov si,offset tmpbuf
- jmp crun ; join run cmd from there
- DIRECT ENDP
-
- ; This is the 'HELP' command. It gives a list of the commands
-
- HELP PROC NEAR
- mov kstatus,0 ; global status
- mov ah,cmcfm
- call comnd ; Get a confirm
- jmp r
- mov ah,prstr ; show Quick help summary screen
- ; mov dx,offset qckhlp
- mcmsg qckhlp,cqckhlp
- int dos
- mov ah,conout
- mov dl,trans.escchr ; get Kermit escape character
- add dl,40h ; convert to printable
- push dx ; save it for repeats below
- int dos
- mov ah,prstr
- ; mov dx,offset qckhlp1 ; more help text
- mcmsg qckhlp1,cqckhlp1
- int dos
- mov ah,conout
- pop dx
- push dx
- int dos
- mov ah,prstr
- ; mov dx,offset qckhlp2 ; more help text
- mcmsg qckhlp2,cqckhlp2
- int dos
- pop dx ; recover current escape char
- mov ah,conout
- int dos
- mov ah,prstr
- ; mov dx,offset qckhlp3 ; end of help message
- mcmsg qckhlp3,cqckhlp3
- int dos
- mov ah,coninq ; get a keystroke, quietly
- int dos
- cmp al,'?' ; query mark?
- jne helpx ; ne = no, skip second screen
- mov ah,prstr ; show help summary screen
- mov dx,offset crlf ; a few blank lines
- int dos
- int dos
- int dos
- ; mov dx,offset tophlp ; show usual cryptic help
- mcmsg tophlp,ctophlp
- int dos
- helpx: jmp rskp
- HELP ENDP
-
- ; the version command - print our version number
- prvers proc near
- mov kstatus,0 ; global status
- mov ah,cmcfm
- call comnd
- jmp r
- mov ah,prstr
- mov dx,offset crlf
- int dos
- mov ah,prstr
- mov dx,offset machnam ; print machine name
- int dos
- mov ah,prstr ; Print the version header
- ; mov dx,offset versio
- mcmsg versio, cversio
- int dos
- jmp rskp
- prvers endp
-
- ; the show command
- showcmd proc near
- mov kstatus,0 ; global status
- mov ah,cmkey
- mov dx,offset shotab
- xor bx,bx ; no canned help
- call comnd
- jmp r
- jmp bx ; execute the handler
- showcmd endp
-
- ; the type command - type out a file
- typec proc near
- mov kstatus,0 ; global status
- mov si,offset typcmd ; type command
- mov di,offset tmpbuf
- call strcpy
- mov dx,offset tmpbuf
- call strlen ; get its length
- add di,cx ; point at terminator
- mov ah,cmtxt ; parse with cmtxt so we can have paths
- mov bx,di ; next available byte
- ; mov dx,offset filmsg ; In case user wants help.
- mcmsg filmsg, cfilmsg
- call comnd
- jmp r
- cmp ah,0 ; any text given?
- jne typec1 ; ne = yes
- mov ah,prstr
- ; mov dx,offset ermes1 ; say need more info
- mcmsg ermes1, cermes1
- int dos
- jmp rskp
- typec1: mov byte ptr [bx],0 ; plant terminator
- mov si,offset tmpbuf
- jmp crun ; join run cmd from there
- typec endp
-
- ; PUSH to DOS (run another copy of Command.com or equiv)
- ; entry fpush (fast push...) pushes without waiting for a confirm
- ; returns rskp
- dopush proc near
- dopus1: mov ah,cmcfm
- call comnd
- jmp r
- nop
- fpush: mov si,offset tmpbuf ; a dummy buffer
- mov byte ptr [si],0 ; plant terminator
- jmp short crun4 ; go run it
- dopush endp
-
- ; Run a program from within Kermit
- RUN PROC NEAR
- mov ah,cmtxt ; Get program name and any arguments
- mov bx,offset tmpbuf ; place for user's text
- ; mov dx,offset runmsg ; In case user wants help
- mcmsg runmsg, crunmsg
- call comnd
- jmp r
- nop
- cmp ah,0 ; byte count
- jne run2 ; ne = have program name
- mov ah,prstr ; else complain
- ; mov dx,offset ermes1 ; need more info
- mcmsg ermes1,cermes1
- int dos
- jmp rskp
- run2: mov si,offset tmpbuf ; source of text
- jmp crun
- RUN ENDP
-
- ; crun - run an arbitrary program. Rewritten by [jrd]
- ; Enter with ordinary asciiz command in si (such as Dir *.asm)
- ; Append a c/r and a null terminator and then ask command.com to do it
- CRUN proc near
- mov ah,prstr ; output crlf before executing comnd. [lba]
- mov dx,offset crlf ; [lba]
- int dos ; display it. [lba]
- mov di,offset tmpbuf ; where to put full command line text
- cmp si,di ; same place?
- je crun1 ; e = yes, don't copy ourself
- call strcpy ; si holds source text
- crun1: mov si,offset slashc ; DOS command begins with slashc area
- mov dx,offset slashc+1 ; si points to /c part of command line
- call strlen ; get its length into cx
- push bx
- mov bx,dx
- add bx,cx
- mov byte ptr [bx],cr ; end string with a c/r for dos
- inc cx ; count the c/r
- mov byte ptr [bx+1],0 ; and terminate
- pop bx
- mov [si],cl ; put length of argument here
- crun4: mov exearg+2,si ; pointer to argument string
- mov exearg+4,ds ; segment of same
- cmp lclsusp,0 ; sys dependent routine to call
- je crun5 ; e = none
- mov bx,lclsusp ; address to call
- call bx ; call sys dependent suspend routine
- crun5: call serrst ; reset serial port (if active)
- mov es,psp ; point to psp again
- mov exearg+8,es ; segment of psp, use our def fcb's
- mov exearg+12,es ; segment of psp, ditto, for fcb 2
- mov ax,es:word ptr [env] ; get environment ptr
- mov exearg,ax ; put into argument block
- mov ax,ds
- mov es,ax ; put es segment back
- mov bx,offset exearg ; es:bx points to exec parameter block
- mov dx,offset cmspbuf ; always use command.com
- mov al,0 ; load and execute..
- mov ah,exec
- mov ssave,sp ; save stack ptr
- int dos ; go run the program
- mov ax,datas
- mov ds,ax ; reset data segment
- mov es,ax ; and extra segment
- mov ax,cstack
- mov ss,ax ; and stack segment
- mov sp,ssave ; restore stack ptr
- pushf ; save flags
- mov ah,setdma
- mov dx,offset buff
- int dos ; restore dma address!!
- popf ; recover flags
- jc crun8 ; c = error, handle
- cmp lclrest,0 ; sys dependent routine to call
- je crun9 ; e = none
- mov bx,lclrest ; get routine's address
- call bx ; call sys dependent restore routine
- crun9: jmp rskp ; ok, return
- crun8: mov ah,prstr
- ; mov dx,offset erms37
- mcmsg erms37,cerms37
- int dos
- mov kstatus,8 ; global status
- jmp rskp
- CRUN ENDP
-
- ; Replace Int 23h and Int 24h with our own handlers
- ; Revised to ask DOS for original interrupt vector contents, as suggested by
- ; Jack Bryans. 9 Jan 1986 jrd
- ; Modified again 30 August 1986 [jrd]
- SETINT PROC NEAR
- push es ; save registers
- push bx
- mov al,23H ; desired interrupt vector (^C)
- mov ah,35H ; Int 21H, function 35H = Get Vector
- int dos ; get vector in es:bx
- mov in3ad,bx ; save offset address of original vector
- mov in3ad+2,es ; and its segment
- mov al,24h ; DOS critical error, Int 24h
- mov ah,35h
- int dos
- mov word ptr ceadr,bx ; DOS's Critical Error handler, offset
- mov word ptr ceadr+2,es ; and segment address
- push ds ; save ds around next DOS call
- mov ax,cs ; compose full address of ^C routine
- mov ds,ax ; Offset is the code segment
- mov dx,offset intbrk ; and main address is intbrk
- mov al,23H ; On ^C, goto intbrk
- mov ah,25H ; set interrupt address from ds:dx
- int dos
- mov dx,offset dosce ; replacement Critical Error handler
- mov al,24h ; interrupt 24h
- mov ah,25h ; replace it
- int dos
- pop ds
- pop bx
- pop es
- ret
- SETINT ENDP
-
- ; Control Break, Interrupt 23h replacement
- ; Always return with a Continue (vs Abort) condition since Kermit will cope
- ; with failures. [jrd]
- intbrk: push ax
- push ds
- mov ax,datas ; get Kermit's data segment
- mov ds,ax
- mov flags.cxzflg,'C' ; Say we saw a ^C
- mov pack.state,'A' ; Set the state to abort
- pop ds
- pop ax
- iret ; return to caller in a Continue condition
-
- ; Kermit's DOS Critical Error Handler, Int 24h. [jrd]
- ; Needed to avoid aborting Kermit with the serial port interrupt active and
- ; the Control Break interrupt redirected. See the DOS Tech Ref Manual for
- ; a start on this material; it is neither complete nor entirely accurate
- ; The stack is the Kermit's stack, the data segment is unknown, interrupts
- ; are off, and the code segment is Kermit's. Note: some implementations of
- ; MS DOS may leave us in DOS's stack. Called by a DOS Int 21h function
- dosce: test ah,80h ; block device (disk drive)?
- jnz dosce1 ; nz = no; serial device, memory, etc
- mov al,3 ; tell DOS to Fail the Int 21h call
- iret ; return to DOS
- dosce1: add sp,6 ; pop IP, CS, Flags regs, from DOS's Int 24h
- pop ax ; restore original callers regs existing
- pop bx ; just before doing Int 21h call
- pop cx
- pop dx
- pop si
- pop di
- pop bp
- pop ds
- pop es
- mov al,0ffh ; signal failure (usually) the DOS 1.x way
- push ax ; Kermit's IP, CS, and Flags are on the stack
- push bp ; all ready for an iret, but first a word ..
- mov bp,sp
- mov ax,ss:[bp+8] ; get Kermit's flags word
- or ax,1 ; set the carry bit, signal failure DOS 2+ way
- mov ss:[bp+8],ax ; store new flags back in the stack
- pop bp ; this avoids seeing the Interrupt flag bit
- pop ax
- iret ; return to user, simulate return from Int 21h
-
- ISFILE PROC NEAR
- ; Enter with ds:ax pointing at asciiz filename string
- ; Returns carry set if the file pointed to by ax does not exist, else reset
- ; Returns status byte, fstat, with DOS status and high bit set if major error
- ; Does a search-for-first to permit paths and wild cards
- ; Examines All kinds of files (ordinary, subdirs, vol labels, system,
- ; and hidden). Upgraded to All kinds on 27 Dec 1985. Revised 30 Aug 86 [jrd]
- ; All registers are preserved
-
- push dx ; save regs
- push cx
- push ax
- mov byte ptr filtst.dta+21,0 ; clear old attribute bits
- mov byte ptr filtst.fname,0 ; clear any old filenames
- mov filtst.fstat,0 ; clear status byte
- mov cx,3fH ; look at all kinds of files
- mov dx,offset filtst.dta ; own own temporary dta
- mov ah,setdma ; set to new dta
- int dos
- pop dx ; get ax (filename string ptr)
- push dx ; save it again
- mov ah,first2 ; search for first
- int dos
- pushf ; save flags
- mov dx,offset buff ; reset dma
- mov ah,setdma
- int dos
- popf ; recover flags
- jnc isfil1 ; nc = file found
- mov filtst.fstat,al ; record DOS status
- cmp al,2 ; just "File Not Found"?
- je isfil2 ; e = yes
- cmp al,3 ; "Path not found"?
- je isfil2 ; e = yes
- cmp al,18 ; "No more files"?
- je isfil2 ; e = yes
- or filtst.fstat,80h ; set high bit for more serious error
- jmp isfil2
- isfil1: cmp byte ptr filtst.fname,0 ; did DOS fill in a name?
- jne isfil3 ; nz = yes
- isfil2: stc ; else set carry flag bit
- isfil3: pop ax
- pop cx
- pop dx
- ret ; DOS sets carry if file not found
- ISFILE ENDP
-
- ; initialize memory usage by returning to DOS anything past the end of kermit
- memini proc near
- push es
- mov es,psp ; address psp segment again
- mov bx,offset msfinal + 15 ; end of pgm + roundup
- mov cl,4
- shr bx,cl ; compute # of paragraphs in last seg
- mov ax,datas ; last segment
- sub ax,psp ; minus beginning
- add bx,ax ; # of paragraphs occupied
- mov ah,setblk
- int dos
- jc memin1
- pop es
- ret
- memin1: pop es
- ; mov dx,offset ermes2
- mcmsg ermes2,cermes2
- mov ah,prstr
- int dos ; complain
- jmp krmend ; and just exit..
- memini endp
-
- ; Allocate memory. Passed a memory size in ax, allocates that many
- ; bytes (actually rounds up to a paragraph) and returns its SEGMENT in ax
- ; The memory is NOT initialized. Written by [jrd] to allow memory to
- ; be allocated anywhere in the 1MB address space
- sbrk proc near ; K & R, please forgive us
- mov bx,ax ; bytes wanted
- add bx,15 ; round up
- mov cl,4
- shr bx,cl ; convert to # of paragraphs
- mov ah,alloc ; DOS memory allocator
- int dos
- jc sbrkx ; c = fatal
- ret ; and return segment in ax
- ;sbrkx: mov dx,offset mfmsg ; assume not enough memory (ax = 8)
- sbrkx: mcmsg mfmsg, cmfmsg
- cmp ax,7 ; corrupted memory (ax = 7)?
- jne sbrkx1 ; ne = no
- ; mov dx,offset mf7msg ; corrupted memory found
- mcmsg mf7msg, cmf7msg
- sbrkx1: mov ah,prstr
- int dos
- jmp krmend ; exit Kermit now
- sbrk endp
-
-
- ; Jumping to this location is like retskp. It assumes the instruction
- ; after the call is a jmp addr
-
- RSKP PROC NEAR
- pop bp
- add bp,3
- push bp
- ret
- RSKP ENDP
-
- ; Jumping here is the same as a ret
-
- R PROC NEAR
- ret
- R ENDP
-
- code ends ; End of code section
- end start
-